home
***
CD-ROM
|
disk
|
FTP
|
other
***
search
/
Libris Britannia 4
/
science library(b).zip
/
science library(b)
/
MATH
/
SPECTR20.ZIP
/
MAKDAT.FOR
< prev
next >
Wrap
Text File
|
1992-04-28
|
9KB
|
278 lines
* MAKDAT.FOR
* Create a binary data file which
* can be read by the spectrum routine.
* David E. Hess
* Fluid Flow Group - Process Measurements Division
* Chemical Science and Technology Laboratory
* National Institute of Standards and Technology
* April 15, 1992
* This routine reads an ASCII input data file and rewrites
* the data into a binary data file which can be processed by the
* SPECTRUM calculation program. The routine first prompts the
* user for information necessary to create the file header and
* then the rewriting procedure begins. Extensive error checking
* is included in an attempt to make the transformation process as
* painless as possible. Refer to the section in the user's manual
* for further details.
* File Extensions
* ---------------
* .ASC - ASCII input data file (no header, just numbers)
* .DAT - Binary output file (with file header)
* Header Information
* ------------------
* ICHANS : # of channels of data.
* IDELTMS : sampling interval in microseconds.
* IRSIZE : # of bytes in each record.
* N : # of points per record per channel.
* NUMREC : # of records in data file.
* GAIN : array of gain values for each channel
IMPLICIT REAL*4 (A-H,O-Z), INTEGER*2 (I-N)
PARAMETER (NUMI=2,NUMO=3,NMAX=16384)
INTEGER*2 GAIN(0:7)
INTEGER*2 NDATA[ALLOCATABLE,HUGE](:)
INTEGER*4 IRSIZE,IDELTMS
REAL*4 RDATA[ALLOCATABLE,HUGE](:)
LOGICAL*1 INTGER,FLOTNG,ONECHAN,TWOCHAN
CHARACTER INSFX *4 /'.ASC'/, OUTSFX *4 /'.DAT'/
CHARACTER*1 INP,FIRST
CHARACTER*4 INNAM
CHARACTER*8 INFIL,OUTFIL
* Initialize gain array.
GAIN=0
* Integer or floating point data ?
10 WRITE (*,'(/1X,A,A\)') '(I)nteger (2-byte) or ',
+ '(F)loating-point (4-byte) data : '
READ (*,'(A)') INP
IF (INP .EQ. 'i') INP = 'I'
IF (INP .EQ. 'f') INP = 'F'
INTGER=(INP .EQ. 'I')
FLOTNG=(INP .EQ. 'F')
IF (.NOT. INTGER .AND. .NOT. FLOTNG) GO TO 10
* Get # of channels.
20 WRITE (*,'(/1X,A\)') 'Enter # of channels (1 or 2) : '
READ (*,*) ICHANS
ONECHAN=(ICHANS .EQ. 1)
TWOCHAN=(ICHANS .EQ. 2)
IF (.NOT. ONECHAN .AND. .NOT. TWOCHAN) GO TO 20
* Get # of points per record per channel.
WRITE (*,'(/1X,A,I5,A/1X,A,A,I5,A)')
+ 'One channel : Total # points per record <= ',
+ NMAX,'.','Two channels : Total # points per record',
+ ' per channel <= ',NMAX/2,'.'
30 IF (ONECHAN) THEN
WRITE (*,'(/1X,A,A\)') 'Enter # of points per',
+ ' record (power of two) : '
READ (*,*) N
ELSE
WRITE (*,'(/1X,A,A/1X,A\)') 'Enter # of points per',
+ ' record for each channel (power of two).',
+ 'Total # of points per record is double this number : '
READ (*,*) N
ENDIF
* N less than or equal to NMAX error checking.
IF (ONECHAN) NTST=NMAX
IF (TWOCHAN) NTST=NMAX/2
IF (N .GT. NMAX) THEN
WRITE (*,'(/1X,A,A,I5,A)') '# of points per record',
+ ' per channel <= ',NTST,' dummy!'
GO TO 30
ENDIF
* Power of two error checking.
FN=FLOAT(N)
ITST=NINT(ALOG10(FN)/ALOG10(2.0))
ITST2=INT(2**ITST)-N
IF (ITST2 .NE. 0) THEN
WRITE (*,'(/1X,A,I5,A/1X,A)') 'You have entered ',
+ N,' data points.','# data points must be a power of 2.'
GO TO 30
ENDIF
IF (INTGER) IRSIZE=ICHANS*N*2
IF (FLOTNG) IRSIZE=ICHANS*N*4
* Allocate space for NDATA and RDATA arrays.
IF (ONECHAN .AND. INTGER) ALLOCATE (NDATA(N), STAT=IERR)
IF (ONECHAN .AND. FLOTNG) ALLOCATE (RDATA(N), STAT=IERR)
IF (TWOCHAN .AND. INTGER) ALLOCATE (NDATA(2*N), STAT=IERR)
IF (TWOCHAN .AND. FLOTNG) ALLOCATE (RDATA(2*N), STAT=IERR)
IF (IERR .NE. 0)
+ STOP 'Not enough storage for data. Aborting ...'
* Get # of records in data file.
WRITE (*,'(/1X,A/1X,A)')
+ 'One channel : May be EVEN or ODD # of records.',
+ 'Two channels : May be EVEN or ODD # of records.'
WRITE (*,'(/1X,A\)') 'Enter # of records in the data file : '
READ (*,*) NUMREC
* Get the sampling interval.
WRITE (*,'(/1X,A/1X,A/1X,A/1X,A)')
+'One chan : Delta t is spacing between data points.',
+'Two chans : Delta t is spacing between data pts - SAME channel.',
+' Delta t divided by 2 is spacing between data pts',
+' - different channels.'
WRITE (*,'(/1X,A\)') 'Enter sampling interval delta t (secs) : '
READ (*,*) DELT
IDELTMS=NINT(DELT*1.0E+06)
WRITE (*,'( )')
* Set the gain for each channel.
WRITE (*,'(14X,A,5X,A)') ' Voltage Range ','Gain'
WRITE (*,'(14X,A,5X,A)') ' ------------- ','----'
WRITE (*,'(14X,A,5X,A)') '-10.00 to 10.00',' 0 '
WRITE (*,'(14X,A,5X,A)') '- 5.00 to 5.00',' 1 '
WRITE (*,'(14X,A,5X,A)') '- 2.50 to 2.50',' 2 '
WRITE (*,'(14X,A,5X,A)') '- 1.25 to 1.25',' 3 '
WRITE (*,'( )')
DO I=0,ICHANS-1
WRITE (*,'(1X,A,I1,A\)') 'Enter gain for channel ',I,' : '
READ (*,*) GAIN(I)
ENDDO
* Get input file name.
40 WRITE (*,'(/1X,A\)') 'Enter ASCII input file name (4 chars) : '
READ (*,'(A)') INNAM
* Convert to uppercase and check first character alphabetic.
DO J=4,1,-1
FIRST=INNAM(J:J)
IF (ICHAR(FIRST) .GE. 97 .AND. ICHAR(FIRST) .LE. 122) THEN
IHOLD=ICHAR(FIRST)-32
FIRST=CHAR(IHOLD)
INNAM(J:J)=FIRST
ENDIF
ENDDO
IF (ICHAR(FIRST) .LT. 65 .OR. ICHAR(FIRST) .GT. 90) THEN
WRITE (*,'(/1X,A,A,A/1X,A,A,A/1X,A)')
+ 'Filename ',INNAM,' began with',
+ 'the nonalphabetic character ',FIRST,'.',
+ 'Re-enter the filename correctly.'
GO TO 40
ENDIF
INFIL=INNAM // INSFX
OUTFIL=INNAM // OUTSFX
* Put message on screen.
WRITE (*,'(/////////////////////16X,
+ ''D A T A F I L E C R E A T I O N U T I L I T Y'')')
WRITE (*,'(/25X,''Creating '',A,'' now.'')') OUTFIL
* Open input ASCII file.
OPEN (NUMI,FILE=INFIL,STATUS='OLD',ERR=100)
* Open output data file and write header.
OPEN (NUMO,FILE=OUTFIL,STATUS='UNKNOWN',ACCESS='SEQUENTIAL',
+ FORM='BINARY',ERR=110)
WRITE (NUMO) ICHANS,IRSIZE,NUMREC,IDELTMS
WRITE (NUMO) (GAIN(I),I=0,7)
* Display header information.
WRITE (*,'(/25X,A,I1)') '# channels = ',ICHANS
WRITE (*,'(25X,A,I5,A)') 'record size = ',IRSIZE,' bytes'
WRITE (*,'(25X,A,I5)') '# of records = ',NUMREC
WRITE (*,'(25X,A,I5,A/)') 'delta t = ',IDELTMS,' microseconds'
DO J=1,NUMREC
* Display record count.
IF (J .EQ. 1) THEN
WRITE (*,50) J
50 FORMAT (25X,'Record ',I4.4)
ELSE
WRITE (*,60) J
60 FORMAT ('+',24X,'Record ',I4.4)
ENDIF
IF (INTGER) THEN
IF (ONECHAN) THEN
READ (NUMI,*,ERR=120,END=140) (NDATA(I), I=1,N)
WRITE (NUMO, ERR=130) (NDATA(I), I=1,N)
ELSE
READ (NUMI,*,ERR=120,END=140) (NDATA(I), I=1,2*N)
WRITE (NUMO, ERR=130) (NDATA(I), I=1,2*N)
ENDIF
ELSE IF (FLOTNG) THEN
IF (ONECHAN) THEN
READ (NUMI,*,ERR=120,END=140) (RDATA(I), I=1,N)
WRITE (NUMO, ERR=130) (RDATA(I), I=1,N)
ELSE
READ (NUMI,*,ERR=120,END=140) (RDATA(I), I=1,2*N)
WRITE (NUMO, ERR=130) (RDATA(I), I=1,2*N)
ENDIF
ENDIF
ENDDO
CLOSE (NUMI,STATUS='KEEP')
CLOSE (NUMO,STATUS='KEEP')
WRITE (*,'( )')
STOP ' Program terminated successfully.'
* Problem opening input ASCII file.
100 WRITE (*,'(/25X,A/)') 'Problem opening input ASCII file.'
STOP ' Program terminated unsuccessfully.'
* Problem opening output data file.
110 WRITE (*,'(/25X,A/)') 'Problem opening output data file.'
STOP ' Program terminated unsuccessfully.'
* Problem reading input ASCII file.
120 WRITE (*,'(/25X,A/)') 'Problem reading input ASCII file.'
CLOSE (NUMI,STATUS='KEEP')
CLOSE (NUMO,STATUS='KEEP')
STOP ' Program terminated unsuccessfully.'
* Problem writing output data file.
130 WRITE (*,'(/25X,A/)') 'Problem writing output data file.'
CLOSE (NUMI,STATUS='KEEP')
CLOSE (NUMO,STATUS='KEEP')
STOP ' Program terminated unsuccessfully.'
* Problem : reached end of file marker reading input ASCII file.
140 WRITE (*,'(/25X,A/)') 'Problem : reached end of file marker',
+ ' reading input ASCII file.'
CLOSE (NUMI,STATUS='KEEP')
CLOSE (NUMO,STATUS='KEEP')
STOP ' Program terminated unsuccessfully.'
END